open and read a ini file
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | fileName | |||
type(IniList), | intent(out) | :: | iniDB |
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
integer(kind=long), | public | :: | i | ||||
character(len=stringLen), | public | :: | inLine | ||||
integer(kind=short), | public | :: | unit_id |
SUBROUTINE IniOpenFileName & ! (fileName, iniDB) IMPLICIT NONE ! subroutine arguments ! Scalar arguments with intent(in): CHARACTER (LEN = *), INTENT(IN) :: fileName ! Array arguments with intent(out): TYPE (IniList), INTENT(OUT) :: iniDB ! Local Scalars: CHARACTER (LEN = stringLen) :: inLine INTEGER (KIND = long) :: i INTEGER (KIND = short) :: unit_id !------------end of declaration------------------------------------------------ !------------------------------------------------------------------------------ ![1.0] Inizialization: !------------------------------------------------------------------------------ iniDB % nOfSections = 0 iniDB % nOfSubSections = 0 iniDB % numKeys = 0 numKeys = 0 unit_id = GetUnit () OPEN(UNIT = unit_id, FILE = fileName, FORM = 'formatted', & STATUS = 'old', IOSTAT = ios) IF (ios > 0) THEN CALL Catch ('error', 'IniLib', & 'error in opening file: ' , & code = openFileError, argument = filename ) ENDIF !count number of keys in file iniDB % numKeys = IniCountKeys (unit_id) !allocate space ALLOCATE ( iniDB % keys ( iniDB % numKeys ) ) ALLOCATE ( iniDB % vals ( iniDB % numKeys ) ) ALLOCATE ( iniDB % sectionName ( iniDB % numKeys ) ) ALLOCATE ( iniDB % subSectionName ( iniDB % numKeys ) ) ALLOCATE ( iniDB % sectionBegin ( iniDB % numKeys ) ) ALLOCATE ( iniDB % sectionEnd ( iniDB % numKeys ) ) ALLOCATE ( iniDB % subSectionBegin ( iniDB % numKeys ) ) ALLOCATE ( iniDB % subSectionEnd ( iniDB % numKeys ) ) iniDB % keys = '' iniDB % vals = '' iniDB % sectionName = '' iniDB % subSectionName = '' iniDB % sectionBegin = 0 iniDB % sectionEnd = 0 iniDB % subSectionBegin = 0 iniDB % subSectionEnd = 0 inSection = .FALSE. inSubSection = .FALSE. !------------------------------------------------------------------------------ ![2.0] Parse ini file to the end of file: !------------------------------------------------------------------------------ REWIND (unit_id) DO READ (unit_id,'(a)',IOSTAT = ios) inLine IF (ios < 0) THEN !end of file encountered CALL CheckClosure(iniDB) CLOSE (unit_id) EXIT ENDIF IF (inLine /= '') CALL IniAddLine(inLine, iniDB) END DO !------------------------------------------------------------------------------ ![3.0] close ini file: !------------------------------------------------------------------------------ CLOSE (unit_id) RETURN END SUBROUTINE IniOpenFileName